1/* <Dangerous Waters>, by <Anwesha Das>. */
    2
    3:- dynamic i_am_at/1, at/2, holding/1, armed/1, seen/1, floor_at/1, not_seen/1, floor_at/1, not_picked/1, time/1, count/1.    4:- retractall(at(_, _)), retractall(i_am_at(_)), retractall(armed(_)), retractall(not_seen(_)), retractall(floor_at(_)), retractall(not_picked(_)), retractall(count(_)), retractall(time(_)).    5
    6/* This tells your current location. */
    7i_am_at(deck).
    8floor_at(deck).
    9
   10time(90).
   11count(_).
   12
   13/* Directions */
   14path(corridor, e, boiler_room):- holding(chloroform), count(Z), retract(count(Z)), assert(count(3)), !.
   15
   16path(corridor, e, boiler_room):- retract(floor_at(_)), assert(floor_at(boiler_room)), retract(i_am_at(_)), assert(i_am_at(corridor)),  write('You see two men with guns sitting outside the room. You don''t have anything to attack the guards or defend yourself!!!'), nl, 
   17				 write('Unfortunately, customs did not allow you to carry your gun with you on the ship. So you have to find a weapon on the ship itself.'), nl,
   18				 write('Aah! Idea! Maybe you can steal some chloroform from the medical clinic on board (which, as far as you remember, is on the deck), '),
   19				 write('and use it incapacitate the guards!'), nl, !, fail.
   20
   21path(deck, w, stairs) :- count(Z), retract(count(Z)), assert(count(2)).
   22path(deck, s, elevator) :- count(Z), retract(count(Z)), assert(count(5)).
   23path(deck, n, office) :- count(Z), retract(count(Z)), assert(count(5)).
   24path(deck, e, clinic) :- count(Z), retract(count(Z)), assert(count(5)).
   25
   26path(stairs, f, room) :- count(Z), retract(count(Z)), assert(count(8)). 
   27path(stairs, b, corridor) :- count(Z), retract(count(Z)), assert(count(10)).
   28path(stairs, d, deck) :- count(Z), retract(count(Z)), assert(count(10)).
   29
   30path(clinic, n, stairs) :- count(Z), retract(count(Z)), assert(count(6)).
   31path(clinic, s, elevator) :- count(Z), retract(count(Z)), assert(count(8)).
   32path(clinic, w, office):- count(Z), retract(count(Z)), assert(count(5)).
   33
   34path(elevator, d, deck) :- count(Z), retract(count(Z)), assert(count(8)).
   35path(elevator, b, corridor) :- count(Z), retract(count(Z)), assert(count(9)).
   36path(elevator, f, room) :- count(Z), retract(count(Z)), assert(count(5)).
   37
   38path(room, w, stairs) :- count(Z), retract(count(Z)), assert(count(3)).
   39path(room, n, elevator) :- count(Z), retract(count(Z)), assert(count(4)).
   40
   41path(office, s, elevator) :- count(Z), retract(count(Z)), assert(count(8)).
   42path(office, n, stairs) :- count(Z), retract(count(Z)), assert(count(4)).
   43path(office, e, clinic) :- count(Z), retract(count(Z)), assert(count(5)).
   44path(office, w, baggage_hold) :- count(Z), retract(count(Z)), assert(count(7)).
   45
   46path(baggage_hold, e, office) :- count(Z), retract(count(Z)), assert(count(7)).
   47
   48path(corridor, w, elevator) :- count(Z), retract(count(Z)), assert(count(1)).
   49path(boiler_room, w, corridor) :- count(Z), retract(count(Z)), assert(count(3)).
   50
   51/* Locations of objects */
   52at(case, boiler_room).
   53at(keypass, office).
   54at(chloroform, clinic).
   55at(toolkit, baggage_hold).
   56at(laptop, room).
   57
   58
   59/* This fact specifies that the bomb is armed. */
   60
   61armed(bomb).
   62
   63/* This fact specifies that the footage is not seen. */
   64not_seen(footage).
   65
   66/* This fact specifies that the lock is not picked. */
   67not_picked(lock).
   68
   69
   70
   71/* These rules describe how to pick up an object. */
   72
   73take(X) :-
   74        holding(X),
   75        write('You''re already holding it!'),
   76        !, nl.
   77
   78take(X) :-
   79        i_am_at(Place),
   80        at(X, Place),
   81        retract(at(X, Place)),
   82        assert(holding(X)),
   83        write('OK.'),
   84        nl, !.
   85
   86take(_) :-
   87        write('I don''t see it here.'),
   88        nl.
   89
   90 
   91/* These rules describe how to toss the choloroform */
   92
   93toss :- i_am_at(boiler_room),
   94	holding(chloroform),
   95        write('The guards have fainted. The coast is clear. Quick, swipe the keypass at the door to enter. '), !,
   96        nl.
   97
   98toss :- holding(chloroform),
   99	write(' You can''t toss it here! Save it for the men guarding the bomb!'), !,
  100	nl.
  101
  102toss :- write(' There is nothing to toss!'), 
  103	nl.
  104
  105/* This rule describes how to swipe the keypass */
  106swipe :- holding(keypass), i_am_at(boiler_room), write('You are now inside the boiler room. You hear ticking noise coming from the black case infront of you. Open it quick!'), !, nl.
  107
  108/* This rule tells the time */
  109time :- time(T), write(T), write(' min(s) remaining! '), nl.
  110
  111/* These rules describe how to disarm the bomb */
  112disarm :- i_am_at(boiler_room),
  113	write('The bomb has been disarmed!!!! Congratulations! You just saved the lives of 800 people! '), nl, nl,
  114	retract(armed(bomb)), !,
  115	finish,
  116        nl.
  117
  118disarm :- write('You have to get to the bomb first to disarm it!! Hurry!!'), !,
  119	nl.
  120
  121
  122/* These rules describe how to open an object */
  123open :- i_am_at(baggage_hold),
  124	write('You open the bag and can see the toolkit'), !,
  125	nl.
  126
  127open :- i_am_at(boiler_room),
  128	write('You open the case and see the bomb. Hurry!! Disarm it quickly before it goes off!!!!!'), !,
  129	nl.
  130
  131open :- i_am_at(clinic),
  132	write('You open the cabinet and spot the bottle of chloroform.'), !, nl.
  133
  134open :- write('There is nothing to open!'), !,
  135	nl.
  136
  137/* These rules tells how to connect phone to laptop */
  138connect :- i_am_at(room), 
  139	write('You see the footage, which shows the Captain going to the boiler room, swiping his all access keypass and putting a black case in there.'), nl,
  140	write('You decide your next task should be to steal the keypass from the Captain''s office up on the deck!'), nl, nl,
  141	write('You see the stairs to your west and the elevator to the north.'), nl,
  142	retract(not_seen(footage)), !, nl. 
  143
  144connect :- write('There is nothing to connect!'), !, nl.
  145
  146/* This rule tells how to pick a lock */
  147pick :- i_am_at(office), write('You are now inside the captain''s office. It is a mess! Looks like someone went through it in a hurry. You see an empty safe and a ripped up sofa.'), nl, nl,
  148	write('You see the keypass you need lying on the table infront of you.'), !, nl.
  149
  150/* Maps */
  151map :- floor_at(deck), i_am_at(office), write(' North - Stairs '), nl, write(' East - Medical Clinic '), nl, write(' West - Baggage Hold '), nl, write(' South - Elevator '), !, nl.
  152map :- floor_at(deck), i_am_at(baggage_hold), write(' East - Captain''s Office '), !, nl.
  153map :- floor_at(deck), i_am_at(clinic), write(' North - Stairs '), nl, write(' West - Captain''s Office '), nl, write(' South - Elevator '), !, nl.	
  154map :- floor_at(deck), i_am_at(deck), write(' North - Captain''s Office '), nl, write(' East - Medical Clinic '), nl, write(' West - Stairs '), nl, write(' South - Elevator '), !, nl.
  155map :- floor_at(first), i_am_at(room), write(' North - Elevator '), nl, write(' West - Stairs '), !, nl.
  156map :- floor_at(boiler_room), i_am_at(corridor), write(' West - Elevator '), nl, write(' East - Boiler Room '), !, nl.
  157map :- floor_at(boiler_room), i_am_at(boiler_room), write(' West - Corridor '), !, nl.
  158
  159/* These rules define the direction letters as calls to go/1. */
  160
  161n :- go(n).
  162
  163s :- go(s).
  164
  165e :- go(e).
  166
  167w :- go(w).
  168
  169d :- go(d).
  170
  171f :- go(f).
  172
  173b :- go(b).
  174
  175
  176/* This rule tells how to move in a given direction. */
  177
  178go(Direction) :-
  179        i_am_at(Here),
  180        path(Here, Direction, There),
  181	time(X), X > 0, count(Z),
  182	retract(i_am_at(Here)),
  183        assert(i_am_at(There)),
  184	retract(time(X)), 
  185	Y is X-Z, 
  186	assert(time(Y)),
  187        Y>0, describe(There), nl, write(Y), write(' min(s) remaining!'), !, nl.
  188
  189go(_) :- time(X), X =< 0, nl, nl, write('OH NO!! 90 minutes are up! Bomb explodes in... 3...2...1.... BOOOOM!'), finish, !, fail.
  190
  191go(_) :- write('You can''t go that way.'), !, nl.
  192
  193
  194/* This rule tells how to look about you. */
  195
  196look :-
  197        i_am_at(Place),
  198        notice_objects_at(Place),
  199	fail, nl.
  200
  201
  202/* These rules set up a loop to mention all the objects
  203   in your vicinity. */
  204
  205notice_objects_at(Place) :-
  206        at(X, Place),
  207        write('There is a '), write(X), write(' here.'), nl,
  208        fail.
  209
  210notice_objects_at(_).
  211
  212
  213finish :-
  214        nl, nl,
  215        write('The game is over. Please enter the "halt." command.'), 
  216        nl.
  217
  218i :- holding(X), write(X), nl, fail.
  219
  220
  221/* This rule just writes out game instructions. */
  222
  223instructions :-
  224        nl,
  225        write('Enter commands using standard Prolog syntax.'), nl,
  226        write('Available commands are:'), nl,
  227        write('start.             	 -- to start the game.'), nl,
  228        write('n.  s.  e.  w. d. f. b.	 -- to go in that direction.'), nl,
  229	write('connect.      		 -- to connect phone to laptop.'), nl, 
  230	write('open.			 -- to open the bag, cabinet and the black case.'), nl,       
  231	write('take(Object).      	 -- to pick up an object.'), nl,
  232	write('pick.			 -- to pick the lock.'), nl,	
  233        write('toss.      		 -- to toss the chloroform.'), nl,
  234	write('swipe.      		 -- to open the boiler room door.'), nl,
  235	write('time.		         -- to tell you the time remaining till the bomb goes off.'), nl,
  236	write('disarm.		         -- to disarm the bomb.'), nl,
  237        write('instructions.     	 -- to see this message again.'), nl,
  238	write('map.			 -- to view a map of the floor you are on.'), nl,
  239        write('i.			 -- to view an inventory of what all you are holding.'), nl,	
  240        write('halt.            	 -- to end the game and quit.'), nl, nl, nl.
  241        
  242
  243
  244/* This rule prints out instructions and tells where you are. */
  245
  246start :-
  247        instructions, nl, nl, nl,
  248	write('You are Agent Clark, one of the best spies in the world.'), nl,
  249	write('You are currently on vacation on the famous cruise ship, Amadea. '), nl, nl,
  250	write('However, on the third day of the voyage, while you are enjoying the view from the deck, you receive an urgent email from your boss.'), nl,
  251	write('It says the Captain of the Amadea has planted a bomb on the ship and has abandoned it this morning!'), nl,
  252	write('The bomb goes off in 90 MINUTES. You have to disarm the bomb and save the ship and its people before the time is up!'), nl,nl,
  253	write('The email has the security footage attached, which you download, but can''t view it for some reason.'), nl, nl, nl,
  254	write('You need to use your laptop, which is in your room on the first floor, to connect your phone and view the footage!!'), nl, nl,
  255        write('You are on the deck. You see elevator to south. You see stairs to the west.'), !, nl.
  256
  257
  258/* These rules describe the various rooms.  Depending on
  259   circumstances, a room may have more than one description. */
  260		  
  261
  262describe(deck) :-   assert(floor_at(deck)), write('You are on the deck. You see elevator to south. You see stairs to the west. You see the Captain''s office to the north. You also see the medical clinic to your east.'), nl.
  263
  264describe(stairs) :- floor_at(deck), write('You have reached the stairs. You can go down to your room on the first floor(f) or down till the boiler room (b). '), !, nl.
  265describe(stairs) :- floor_at(first), write('You have reached the stairs. You can go up to the deck(d) or down till the boiler room (b). '), !, nl.
  266
  267describe(elevator) :- floor_at(deck), write('You have entered the elevator. You can go down to your room on the first floor(f) or down till the boiler room (b). '), !, nl.
  268describe(elevator) :- floor_at(first), write('You have entered the elevator. You can go up to the deck(d) or down till the boiler room (b) . '), !, nl.
  269describe(elevator) :- floor_at(boiler_room), write('You have entered the elevator. You can go up to the deck(d) or to your room on the first floor (f). '), !, nl.
  270
  271
  272describe(room) :- retract(floor_at(_)), assert(floor_at(first)), write('You are now in your room. You see your laptop. You can connect your phone now to view the footage.'), !, nl.
  273
  274describe(corridor) :- retract(floor_at(_)), assert(floor_at(boiler_room)), retract(i_am_at(_)), assert(i_am_at(corridor)), write('You are now in the corridor. The elevator is to the west. Looking around, you see the boiler room to the east.'), !, nl.
  275
  276describe(boiler_room) :- holding(chloroform), retract(floor_at(_)), assert(floor_at(boiler_room)),
  277			write('The two men are still there. Quick, toss the chloroform bottle at them!'), !, nl.
  278
  279describe(office) :- holding(toolkit), retract(floor_at(_)), assert(floor_at(deck)), not_picked(lock), write('You are back to the Captain''s office door.'), nl,
  280		    write('Quickly pick the lock before somebody notices... hurry!!'), !, nl.
  281		    
  282describe(office) :- retract(floor_at(_)), assert(floor_at(deck)), write('The door is locked. You need to pick the lock. You look for your handy toolkit (which you usually keep in your pocket). But you cannot find it! Then you remember that is inside your checked in suitcase, which is inside the baggage room.'), 
  283		    nl, nl, write('Fortunately on the very first day, you had toured the ship. Thanks to your photographic memory, you remember that the baggage hold is towards the west.'), !,  nl.
  284
  285describe(office) :- retract(floor_at(_)), assert(floor_at(deck)), write('You are now inside the captain''s office. It is a mess! Looks like someone went through it in a hurry. You see an empty safe and a ripped up sofa. You see the elevator to the south, the stairs to the north, the clinic to the east and the baggage hold to the west.'), !, nl.
  286
  287describe(clinic) :- retract(floor_at(_)), assert(floor_at(deck)), 
  288		    write('You are now inside the clinic.'), nl,
  289		    write('Luckily it is empty and the ship doctor is nowhere to be seen. Hopefully you can find some chloroform in here.'), nl, nl,
  290		    write('You see a closed cabinet. You should probably open it.'), !, nl.
  291
  292describe(baggage_hold) :- retract(floor_at(_)), assert(floor_at(deck)), write('You are now inside the baggage hold'), nl, nl,
  293		          write('You can see your bag lying right infront of you. You can open it.'), !, nl